home *** CD-ROM | disk | FTP | other *** search
/ Language/OS - Multiplatform Resource Library / LANGUAGE OS.iso / prolog / prlgbnc1.lha / Bench / nand.pl < prev    next >
Text File  |  1990-07-13  |  20KB  |  563 lines

  1. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  2. %
  3. %  This is a rough approximation to the algorithm presented in:
  4. %
  5. %    "An Algorithm for NAND Decomposition Under Network Constraints,"
  6. %    IEEE Trans. Comp., vol C-18, no. 12, Dec. 1969, p. 1098
  7. %    by E. S. Davidson.
  8. %
  9. %  Written by Bruce Holmer
  10. %
  11. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  12. %
  13. %  I have used the paper's terminology for names used in the program.
  14. %
  15. %  The data structure for representing functions and variables is
  16. %        function(FunctionNumber, TrueSet, FalseSet,
  17. %            ConceivableInputs,
  18. %            ImmediatePredecessors, ImmediateSuccessors,
  19. %            Predecessors, Successors)
  20. %
  21. %
  22. %  Common names used in the program:
  23. %
  24. %    NumVars        number of variables (signal inputs)
  25. %    NumGs        current number of variables and functions
  26. %    Gs        list of variable and function data
  27. %    Gi,Gj,Gk,Gl    individual variable or function--letter corresponds to
  28. %            the subscript in the paper (most of the time)
  29. %    Vector,V    vector from a function's true set
  30. %
  31. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  32.  
  33. main :- main(0).
  34.  
  35. main(N) :-
  36.     init_state(N, NumVars, NumGs, Gs),
  37.     add_necessary_functions(NumVars, NumGs, Gs, NumGs2, Gs2),
  38.     test_bounds(NumVars, NumGs2, Gs2),
  39.     search(NumVars, NumGs2, Gs2).
  40. main(_) :-
  41.     write('Search completed'), nl.
  42.  
  43. %  Test input
  44. %  init_state(circuit(NumInputs, NumOutputs, FunctionList))
  45. init_state(0, 2, 3, [        % 2 input xor
  46.         function(2, [1,2], [0,3], [], [], [], [], []),
  47.         function(1, [2,3], [0,1], [], [], [], [], []),
  48.         function(0, [1,3], [0,2], [], [], [], [], [])
  49.         ]) :-
  50.     update_bounds(_, 100, _).
  51. init_state(1, 3, 4, [        % carry circuit
  52.         function(3, [3,5,6,7], [0,1,2,4], [], [], [], [], []),
  53.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  54.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  55.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  56.         ]) :-
  57.     update_bounds(_, 100, _).
  58. init_state(2, 3, 4, [        % example in paper
  59.         function(3, [1,2,4,6,7], [0,3,5], [], [], [], [], []),
  60.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  61.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  62.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  63.         ]) :-
  64.     update_bounds(_, 100, _).
  65. init_state(3, 3, 4, [        % sum (3 input xor)
  66.         function(3, [1,2,4,7], [0,3,5,6], [], [], [], [], []),
  67.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  68.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  69.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  70.         ]) :-
  71.     update_bounds(_, 100, _).
  72. init_state(4, 3, 5, [        % do sum and carry together
  73.         function(4, [3,5,6,7], [0,1,2,4], [], [], [], [], []),
  74.         function(3, [1,2,4,7], [0,3,5,6], [], [], [], [], []),
  75.         function(2, [4,5,6,7], [0,1,2,3], [], [], [], [], []),
  76.         function(1, [2,3,6,7], [0,1,4,5], [], [], [], [], []),
  77.         function(0, [1,3,5,7], [0,2,4,6], [], [], [], [], [])
  78.         ]) :-
  79.     update_bounds(_, 100, _).
  80. init_state(5, 5, 8, [        % 2 bit full adder
  81.         function(7,        % A2 (output)
  82.             [1,3,4,6,9,11,12,14,16,18,21,23,24,26,29,31],
  83.             [0,2,5,7,8,10,13,15,17,19,20,22,25,27,28,30],
  84.             [], [], [], [], []),
  85.         function(6,        % B2 (output)
  86.             [2,3,5,6,8,9,12,15,17,18,20,21,24,27,30,31],
  87.             [0,1,4,7,10,11,13,14,16,19,22,23,25,26,28,29],
  88.             [], [], [], [], []),
  89.         function(5,        % carry-out (output)
  90.             [7,10,11,13,14,15,19,22,23,25,26,27,28,29,30,31],
  91.             [0,1,2,3,4,5,6,8,9,12,16,17,18,20,21,24],
  92.             [], [], [], [], []),
  93.         function(4,        % carry-in
  94.             [16,17,18,19,20,21,22,23,24,25,26,27,28,29,30,31],
  95.             [0,1,2,3,4,5,6,7,8,9,10,11,12,13,14,15],
  96.             [], [], [], [], []),
  97.         function(3,        % B1 input
  98.             [8,9,10,11,12,13,14,15,24,25,26,27,28,29,30,31],
  99.             [0,1,2,3,4,5,6,7,16,17,18,19,20,21,22,23],
  100.             [], [], [], [], []),
  101.         function(2,        % B0 input
  102.             [4,5,6,7,12,13,14,15,20,21,22,23,28,29,30,31],
  103.             [0,1,2,3,8,9,10,11,16,17,18,19,24,25,26,27],
  104.             [], [], [], [], []),
  105.         function(1,         % A1 input
  106.             [2,3,6,7,10,11,14,15,18,19,22,23,26,27,30,31],
  107.             [0,1,4,5,8,9,12,13,16,17,20,21,24,25,28,29],
  108.             [], [], [], [], []),
  109.         function(0,        % A0 input
  110.             [1,3,5,7,9,11,13,15,17,19,21,23,25,27,29,31],
  111.             [0,2,4,6,8,10,12,14,16,18,20,22,24,26,28,30],
  112.             [], [], [], [], [])
  113.         ]) :-
  114.     update_bounds(_, 21, _).
  115.  
  116.  
  117. %  Iterate over all the TRUE vectors that need to be covered.
  118. %  If no vectors remain to be covered (select_vector fails), then
  119. %  the circuit is complete (printout results, update bounds, and
  120. %  continue search for a lower cost circuit).
  121. search(NumVars, NumGsIn, GsIn) :-
  122.     select_vector(NumVars, NumGsIn, GsIn, Gj, Vector), !,
  123.     cover_vector(NumVars, NumGsIn, GsIn, Gj, Vector, NumGs, Gs),
  124.     add_necessary_functions(NumVars, NumGs, Gs, NumGsOut, GsOut),
  125.     test_bounds(NumVars, NumGsOut, GsOut),
  126.     search(NumVars, NumGsOut, GsOut).
  127. search(NumVars, NumGs, Gs) :-
  128.     output_results(NumVars, NumGs, Gs),
  129.     update_bounds(NumVars, NumGs, Gs),
  130.     fail.
  131.  
  132. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  133. %  Given the current solution, pick the best uncovered TRUE vector
  134. %  for covering next.
  135. %  The selected vector is specified by its vector number and function.
  136. %  Select_vector fails if all TRUE vectors are covered.
  137. %  Select_vector is determinant (gives only one solution).
  138. select_vector(NumVars, NumGs, Gs, Gj, Vector) :-
  139.     select_vector(Gs, NumVars, NumGs, Gs,
  140.         dummy, 0, nf, 999, Gj, Vector, Type, _), !,
  141.     \+ Type = cov,
  142.     \+ Type = nf.
  143.  
  144. % loop over functions
  145. select_vector([Gk|_], NumVars, _, _, Gj, V, Type, N, Gj, V, Type, N) :-
  146.     function_number(Gk, K),
  147.     K < NumVars.
  148. select_vector([Gk|Gks], NumVars, NumGs, Gs,
  149.         GjIn, Vin, TypeIn, Nin, GjOut, Vout, TypeOut, Nout) :-
  150.     function_number(Gk, K),
  151.     K >= NumVars,
  152.     true_set(Gk, Tk),
  153.     select_vector(Tk, Gk, NumVars, NumGs, Gs,
  154.         GjIn, Vin, TypeIn, Nin, Gj, V, Type, N),
  155.     select_vector(Gks, NumVars, NumGs, Gs,
  156.         Gj, V, Type, N, GjOut, Vout, TypeOut, Nout).
  157.     
  158. % loop over vectors
  159. select_vector([], _, _, _, _, Gj, V, Type, N, Gj, V, Type, N).
  160. select_vector([V|Vs], Gk, NumVars, NumGs, Gs,
  161.         GjIn, Vin, TypeIn, Nin, GjOut, Vout, TypeOut, Nout) :-
  162.     vector_cover_type(NumVars, Gs, Gk, V, Type, N),
  163.     best_vector(GjIn, Vin, TypeIn, Nin,
  164.             Gk, V, Type, N,
  165.             Gj2, V2, Type2, N2),
  166.     select_vector(Vs, Gk, NumVars, NumGs, Gs,
  167.         Gj2, V2, Type2, N2, GjOut, Vout, TypeOut, Nout).
  168.  
  169. vector_cover_type(NumVars, Gs, Gj, Vector, Type, NumCovers) :-
  170.     immediate_predecessors(Gj, IPs),
  171.     conceivable_inputs(Gj, CIs),
  172.     false_set(Gj, Fj),
  173.     cover_type1(IPs, Gs, Vector, nf, 0, T, N),
  174.     cover_type2(CIs, Gs, NumVars, Fj, Vector, T, N, Type, NumCovers).
  175.  
  176. cover_type1([], _, _, T, N, T, N).
  177. cover_type1([I|IPs], Gs, V, TypeIn, Nin, TypeOut, Nout) :-
  178.     function(I, Gs, Gi),
  179.     true_set(Gi, Ti),
  180.     \+ set_member(V, Ti), !,
  181.     false_set(Gi, Fi),
  182.     (set_member(V, Fi) ->
  183.         max_type(TypeIn, cov, Type);
  184.         max_type(TypeIn, exp, Type)),
  185.     N is Nin + 1,
  186.     cover_type1(IPs, Gs, V, Type, N, TypeOut, Nout).
  187. cover_type1([_|IPs], Gs, V, TypeIn, Nin, TypeOut, Nout) :-
  188.     cover_type1(IPs, Gs, V, TypeIn, Nin, TypeOut, Nout).
  189.  
  190. cover_type2([], _, _, _, _, T, N, T, N).
  191. cover_type2([I|CIs], Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout) :-
  192.     I < NumVars,
  193.     function(I, Gs, Gi),
  194.     false_set(Gi, Fi),
  195.     set_member(V, Fi), !,
  196.     max_type(TypeIn, var, Type),
  197.     N is Nin + 1,
  198.     cover_type2(CIs, Gs, NumVars, Fj, V, Type, N, TypeOut, Nout).
  199. cover_type2([I|CIs], Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout) :-
  200.     I >= NumVars,
  201.     function(I, Gs, Gi),
  202.     true_set(Gi, Ti),
  203.     \+ set_member(V, Ti), !,
  204.     false_set(Gi, Fi),
  205.     (set_member(V, Fi) ->
  206.         (set_subset(Fj, Ti) ->
  207.             max_type(TypeIn, fcn, Type);
  208.             max_type(TypeIn, mcf, Type));
  209.         (set_subset(Fj, Ti) ->
  210.             max_type(TypeIn, exf, Type);
  211.             max_type(TypeIn, exmcf, Type))),
  212.     N is Nin + 1,
  213.     cover_type2(CIs, Gs, NumVars, Fj, V, Type, N, TypeOut, Nout).
  214. cover_type2([_|CIs], Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout) :-
  215.     cover_type2(CIs, Gs, NumVars, Fj, V, TypeIn, Nin, TypeOut, Nout).
  216.  
  217. %  The best vector to cover is the one with worst type, or, if types
  218. %  are equal, with the least number of possible covers.
  219. best_vector(dummy, _, _, _, Gj2, V2, Type2, N2, Gj2, V2, Type2, N2) :- !.
  220. best_vector(Gj1, V1, Type1, N1, dummy, _, _, _, Gj1, V1, Type1, N1) :- !.
  221. best_vector(Gj1, V1, Type, N1, Gj2, _, Type, N2, Gj1, V1, Type, N1) :-
  222.     function_number(Gj1, J), function_number(Gj2, J),
  223.     N1 < N2, !.
  224. best_vector(Gj1, _, Type, N1, Gj2, V2, Type, N2, Gj2, V2, Type, N2) :-
  225.     function_number(Gj1, J), function_number(Gj2, J),
  226.     N1 >= N2, !.
  227. best_vector(Gj1, V1, Type, N1, Gj2, _, Type, _, Gj1, V1, Type, N1) :-
  228.     (Type = exp ; Type = var),
  229.     function_number(Gj1, J1), function_number(Gj2, J2),
  230.     J1 > J2, !.
  231. best_vector(Gj1, _, Type, _, Gj2, V2, Type, N2, Gj2, V2, Type, N2) :-
  232.     (Type = exp ; Type = var),
  233.     function_number(Gj1, J1), function_number(Gj2, J2),
  234.     J1 < J2, !.
  235. best_vector(Gj1, V1, Type, N1, Gj2, _, Type, _, Gj1, V1, Type, N1) :-
  236.     \+ (Type = exp ; Type = var),
  237.     function_number(Gj1, J1), function_number(Gj2, J2),
  238.     J1 < J2, !.
  239. best_vector(Gj1, _, Type, _, Gj2, V2, Type, N2, Gj2, V2, Type, N2) :-
  240.     \+ (Type = exp ; Type = var),
  241.     function_number(Gj1, J1), function_number(Gj2, J2),
  242.     J1 > J2, !.
  243. best_vector(Gj1, V1, Type1, N1, _, _, Type2, _, Gj1, V1, Type1, N1) :-
  244.     type_order(Type2, Type1), !.
  245. best_vector(_, _, Type1, _, Gj2, V2, Type2, N2, Gj2, V2, Type2, N2) :-
  246.     type_order(Type1, Type2), !.
  247.  
  248. max_type(T1, T2, T1) :- type_order(T1, T2), !.
  249. max_type(T1, T2, T2) :- \+ type_order(T1, T2), !.
  250.  
  251. %  Order of types
  252.  
  253. type_order(cov, exp).
  254. type_order(cov, var).
  255. type_order(cov, fcn).
  256. type_order(cov, mcf).
  257. type_order(cov, exf).
  258. type_order(cov, exmcf).
  259. type_order(cov, nf).
  260. type_order(exp, var).
  261. type_order(exp, fcn).
  262. type_order(exp, mcf).
  263. type_order(exp, exf).
  264. type_order(exp, exmcf).
  265. type_order(exp, nf).
  266. type_order(var, fcn).
  267. type_order(var, mcf).
  268. type_order(var, exf).
  269. type_order(var, exmcf).
  270. type_order(var, nf).
  271. type_order(fcn, mcf).
  272. type_order(fcn, exf).
  273. type_order(fcn, exmcf).
  274. type_order(fcn, nf).
  275. type_order(mcf, exf).
  276. type_order(mcf, exmcf).
  277. type_order(mcf, nf).
  278. type_order(exf, exmcf).
  279. type_order(exf, nf).
  280. type_order(exmcf, nf).
  281.  
  282. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  283.  
  284. %  Cover_vector will cover the specified vector and
  285. %  generate new circuit information.
  286. %  Using backtracking, all possible coverings are generated.
  287. %  The ordering of the possible coverings is approximately that
  288. %  given in Davidson's paper, but has been simplified.
  289.  
  290. cover_vector(NumVars, NumGsIn, GsIn, Gj, Vector, NumGsOut, GsOut) :-
  291.     immediate_predecessors(Gj, IPs),
  292.     conceivable_inputs(Gj, CIs),
  293.     vector_types(Type),
  294.     cover_vector(Type, IPs, CIs, Gj, Vector, NumVars, NumGsIn, GsIn,
  295.         NumGsOut, GsOut).
  296.     
  297. vector_types(var).
  298. vector_types(exp).
  299. vector_types(fcn).
  300. vector_types(mcf).
  301. vector_types(exf).
  302. vector_types(exmcf).
  303. vector_types(nf).
  304.  
  305. cover_vector(exp, [I|_], _, Gj, V, _, NumGs, GsIn, NumGs, GsOut) :-
  306.     function(I, GsIn, Gi),
  307.     true_set(Gi, Ti),
  308.     \+ set_member(V, Ti),
  309.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  310. cover_vector(exp, [_|IPs], _, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  311.     cover_vector(exp, IPs, _, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  312. cover_vector(var, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  313.     I < NumVars,
  314.     function(I, GsIn, Gi),
  315.     false_set(Gi, Fi),
  316.     set_member(V, Fi),
  317.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  318. cover_vector(var, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  319.     cover_vector(var, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  320. cover_vector(fcn, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  321.     I >= NumVars,
  322.     function(I, GsIn, Gi),
  323.     false_set(Gi, Fi),
  324.     set_member(V, Fi),
  325.     true_set(Gi, Ti),
  326.     false_set(Gj, Fj),
  327.     set_subset(Fj, Ti),
  328.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  329. cover_vector(fcn, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  330.     cover_vector(fcn, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  331. cover_vector(mcf, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  332.     I >= NumVars,
  333.     function(I, GsIn, Gi),
  334.     false_set(Gi, Fi),
  335.     set_member(V, Fi),
  336.     true_set(Gi, Ti),
  337.     false_set(Gj, Fj),
  338.     \+ set_subset(Fj, Ti),
  339.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  340. cover_vector(mcf, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  341.     cover_vector(mcf, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  342. cover_vector(exf, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  343.     I >= NumVars,
  344.     function(I, GsIn, Gi),
  345.     false_set(Gi, Fi),
  346.     \+ set_member(V, Fi),
  347.     true_set(Gi, Ti),
  348.     \+ set_member(V, Ti),
  349.     false_set(Gj, Fj),
  350.     set_subset(Fj, Ti),
  351.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  352. cover_vector(exf, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  353.     cover_vector(exf, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  354. cover_vector(exmcf, _, [I|_], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  355.     I >= NumVars,
  356.     function(I, GsIn, Gi),
  357.     false_set(Gi, Fi),
  358.     \+ set_member(V, Fi),
  359.     true_set(Gi, Ti),
  360.     \+ set_member(V, Ti),
  361.     false_set(Gj, Fj),
  362.     \+ set_subset(Fj, Ti),
  363.     update_circuit(GsIn, Gi, Gj, V, GsIn, GsOut).
  364. cover_vector(exmcf, _, [_|CIs], Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut) :-
  365.     cover_vector(exmcf, _, CIs, Gj, V, NumVars, NumGs, GsIn, NumGs, GsOut).
  366. cover_vector(nf, _, _, Gj, V, NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  367.     NumGsOut is NumGsIn + 1,
  368.     false_set(Gj, Fj),
  369.     new_function_CIs(GsIn,
  370.         function(NumGsIn,Fj,[V],[],[],[],[],[]),
  371.         NumVars, Gs, Gi),
  372.     update_circuit(Gs, Gi, Gj, V, Gs, GsOut).
  373.  
  374.  
  375. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  376.  
  377. update_circuit([], _, _, _, _, []).
  378. update_circuit([function(K,Tk,Fk,CIk,IPk,ISk,Pk,Sk)|GsIn],
  379.         Gi, Gj, V, Gs,
  380.         [function(K,Tko,Fko,CIko,IPko,ISko,Pko,Sko)|GsOut]) :-
  381.     Gi = function(I,_,Fi,_,IPi,ISi,Pi,_),
  382.     Gj = function(J,_,Fj,_,_,_,_,Sj),
  383.     set_union([I], Pi, PiI),
  384.     set_union([J], Sj, SjJ),
  385.     (K = J ->
  386.         set_union(Tk, Fi, Tk2);
  387.         Tk2 = Tk),
  388.     (K = I ->
  389.         set_union(Tk2, Fj, Tk3);
  390.         Tk3 = Tk2),
  391.     ((set_member(K, IPi); set_member(K, ISi)) ->
  392.         set_union(Tk3, [V], Tko);
  393.         Tko = Tk3),
  394.     (K = I ->
  395.         set_union(Fk, [V], Fko);
  396.         Fko = Fk),
  397.     ((set_member(K, Pi); K = I) ->
  398.         set_difference(CIk, SjJ, CIk2);
  399.         CIk2 = CIk),
  400.     ((set_member(I, CIk), set_member(V, Fk)) ->
  401.         set_difference(CIk2, [I], CIk3);
  402.         CIk3 = CIk2),
  403.     (K = I ->
  404.         exclude_if_vector_in_false_set(CIk3, Gs, V, CIk4);
  405.         CIk4 = CIk3),
  406.     (K = J ->
  407.         set_difference(CIk4, [I], CIko);
  408.         CIko = CIk4),
  409.     (K = J ->
  410.         set_union(IPk, [I], IPko);
  411.         IPko = IPk),
  412.     (K = I ->
  413.         set_union(ISk, [J], ISko);
  414.         ISko = ISk),
  415.     (set_member(K, SjJ) ->
  416.         set_union(Pk, PiI, Pko);
  417.         Pko = Pk),
  418.     (set_member(K, PiI) ->
  419.         set_union(Sk, SjJ, Sko);
  420.         Sko = Sk),
  421.     update_circuit(GsIn, Gi, Gj, V, Gs, GsOut).
  422.  
  423. exclude_if_vector_in_false_set([], _, _, []).
  424. exclude_if_vector_in_false_set([K|CIsIn], Gs, V, CIsOut) :-
  425.     function(K, Gs, Gk),
  426.     false_set(Gk, Fk),
  427.     set_member(V, Fk), !,
  428.     exclude_if_vector_in_false_set(CIsIn, Gs, V, CIsOut).
  429. exclude_if_vector_in_false_set([K|CIsIn], Gs, V, [K|CIsOut]) :-
  430.     exclude_if_vector_in_false_set(CIsIn, Gs, V, CIsOut).
  431.  
  432.  
  433. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  434.  
  435. add_necessary_functions(NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  436.     add_necessary_functions(NumVars, NumVars, NumGsIn, GsIn,
  437.                     NumGsOut, GsOut).
  438.  
  439. add_necessary_functions(NumGs, _, NumGs, Gs, NumGs, Gs) :- !.
  440. add_necessary_functions(K, NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  441.     function(K, GsIn, Gk),
  442.     function_type(NumVars, NumGsIn, GsIn, Gk, nf, V), !,
  443.     false_set(Gk, Fk),
  444.     new_function_CIs(GsIn,
  445.         function(NumGsIn,Fk,[V],[],[],[],[],[]),
  446.         NumVars, Gs, Gl),
  447.     function(K, Gs, Gk1),
  448.     update_circuit(Gs, Gl, Gk1, V, Gs, Gs1),
  449.     NumGs1 is NumGsIn + 1,
  450.     K1 is K + 1,
  451.     add_necessary_functions(K1, NumVars, NumGs1, Gs1, NumGsOut, GsOut).
  452. add_necessary_functions(K, NumVars, NumGsIn, GsIn, NumGsOut, GsOut) :-
  453.     K1 is K + 1,
  454.     add_necessary_functions(K1, NumVars, NumGsIn, GsIn, NumGsOut, GsOut).
  455.  
  456. new_function_CIs(GsIn, function(L,Tl,Fl,_,IPl,ISl,Pl,Sl), NumVars,
  457.         [GlOut|GsOut], GlOut) :-
  458.     new_function_CIs(GsIn, L, Fl, NumVars, GsOut, [], CIlo),
  459.     GlOut = function(L,Tl,Fl,CIlo,IPl,ISl,Pl,Sl).
  460.     
  461. new_function_CIs([], _, _, _, [], CIl, CIl).
  462. new_function_CIs([function(K,Tk,Fk,CIk,IPk,ISk,Pk,Sk)|GsIn], L, Fl, NumVars,
  463.         [function(K,Tk,Fk,CIko,IPk,ISk,Pk,Sk)|GsOut], CIlIn, CIlOut) :-
  464.     set_intersection(Fl, Fk, []), !,
  465.     (K >= NumVars ->
  466.         set_union(CIk, [L], CIko);
  467.         CIko = CIk),
  468.     new_function_CIs(GsIn, L, Fl, NumVars, GsOut, [K|CIlIn], CIlOut).
  469. new_function_CIs([Gk|GsIn], L, Fl, NumVars, [Gk|GsOut], CIlIn, CIlOut) :-
  470.     new_function_CIs(GsIn, L, Fl, NumVars, GsOut, CIlIn, CIlOut).
  471.  
  472. function_type(NumVars, NumGs, Gs, Gk, Type, Vector) :-
  473.     true_set(Gk, Tk),
  474.     select_vector(Tk, Gk, NumVars, NumGs, Gs,
  475.         dummy, 0, nf, 999, _, Vector, Type, _).
  476.  
  477. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  478. %  Cost and constraint predicates:
  479.  
  480. % very simple bound for now
  481.  
  482. test_bounds(_, NumGs, _) :-
  483.     access(bound, Bound),
  484.     NumGs < Bound.
  485.  
  486. update_bounds(_, NumGs, _) :-
  487.     set(bound, NumGs).
  488.  
  489. % set and access for systems that don't support them
  490. set(N, A) :-
  491.     (recorded(N, _, Ref) -> erase(Ref) ; true),
  492.     recorda(N, A, _).
  493.  
  494. access(N, A) :-
  495.     recorded(N, A, _).
  496.  
  497. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  498. %  Output predicates:
  499.  
  500. %  for now just dump everything
  501.  
  502. output_results(NumVars, NumGs, Gs) :-
  503.     NumGates is NumGs - NumVars,
  504.     write(NumGates), write(' gates'), nl,
  505.     write_gates(Gs), nl,
  506.     write('searching for a better solution...'), nl, nl.
  507.  
  508. write_gates([]).
  509. write_gates([Gi|Gs]) :-
  510.     function_number(Gi, I),
  511.     write('gate #'), write(I), write(' inputs:   '),
  512.     immediate_predecessors(Gi, IPi),
  513.     write(IPi), nl,
  514.     write_gates(Gs).
  515.  
  516. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  517.  
  518. %  Retrieve the specified function from the function list.
  519. %  function(FunctionNumber, FunctionList, Function).
  520. function(I, [Gi|_], Gi) :- function_number(Gi, I), !.
  521. function(I, [_|Gs], Gi) :- function(I, Gs, Gi).
  522.  
  523. function_number(        function(I,_,_,_,_,_,_,_), I).
  524. true_set(               function(_,T,_,_,_,_,_,_), T).
  525. false_set(              function(_,_,F,_,_,_,_,_), F).
  526. conceivable_inputs(     function(_,_,_,CI,_,_,_,_), CI).
  527. immediate_predecessors( function(_,_,_,_,IP,_,_,_), IP).
  528. immediate_successors(   function(_,_,_,_,_,IS,_,_), IS).
  529. predecessors(           function(_,_,_,_,_,_,P,_), P).
  530. successors(             function(_,_,_,_,_,_,_,S), S).
  531.  
  532. %%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%%
  533. %  Set operations assume that the sets are represented by an ordered list
  534. %  of integers.
  535.  
  536. set_union([],     [],     []).
  537. set_union([],     [X|L2], [X|L2]).
  538. set_union([X|L1], [],     [X|L1]).
  539. set_union([X|L1], [X|L2], [X|L3]) :-        set_union(L1, L2,     L3).
  540. set_union([X|L1], [Y|L2], [X|L3]) :- X < Y, set_union(L1, [Y|L2], L3).
  541. set_union([X|L1], [Y|L2], [Y|L3]) :- X > Y, set_union([X|L1], L2, L3).
  542.  
  543. set_intersection([],     [],     []).
  544. set_intersection([],     [_|_],  []).
  545. set_intersection([_|_],  [],     []).
  546. set_intersection([X|L1], [X|L2], [X|L3]) :-    set_intersection(L1, L2,     L3).
  547. set_intersection([X|L1], [Y|L2], L3) :- X < Y, set_intersection(L1, [Y|L2], L3).
  548. set_intersection([X|L1], [Y|L2], L3) :- X > Y, set_intersection([X|L1], L2, L3).
  549.  
  550. set_difference([],     [],     []).
  551. set_difference([],     [_|_],  []).
  552. set_difference([X|L1], [],     [X|L1]).
  553. set_difference([X|L1], [X|L2], L3) :-            set_difference(L1, L2,     L3).
  554. set_difference([X|L1], [Y|L2], [X|L3]) :- X < Y, set_difference(L1, [Y|L2], L3).
  555. set_difference([X|L1], [Y|L2], L3) :-     X > Y, set_difference([X|L1], L2, L3).
  556.  
  557. set_subset([],     _).
  558. set_subset([X|L1], [X|L2]) :-        set_subset(L1, L2).
  559. set_subset([X|L1], [Y|L2]) :- X > Y, set_subset([X|L1], L2).
  560.  
  561. set_member(X, [X|_]).
  562. set_member(X, [Y|T]) :- X > Y, set_member(X, T).
  563.